home *** CD-ROM | disk | FTP | other *** search
- page ,132
-
- ; (C) Copyright Microsoft Corp. 1991. All rights reserved.
- ;
- ; You have a royalty-free right to use, modify, reproduce and
- ; distribute the Sample Files (and/or any modified version) in
- ; any way you find useful, provided that you agree that
- ; Microsoft has no warranty obligations or liability for any
- ; Sample Application Files which are modified.
-
- .xlist
- include cmacros.inc
- include windows.inc
- .list
-
- externA __WinFlags ; in KERNEL
- externA __AHSHIFT
- externA __AHINCR
-
- LONG struc
- lo dw ?
- hi dw ?
- LONG ends
-
- FARPOINTER struc
- off dw ?
- sel dw ?
- FARPOINTER ends
-
- ; DDA structure
- DDASTRUC struc
- pixCur dw ? ; current X position
- pixXinc dw ? ; amount to add to X (-1, 0, or 1)
- pixSlope dw ? ; BOOL: non-zero if DX <= DY
- pixError dw ? ; current amount of error
- pixErrReset dw ? ; amount to add to update error
- pixRem dw ? ; amount to add to reset error
- DDASTRUC ends
-
-
- smov macro segreg1,segreg2
- push segreg2
- pop segreg1
- endm
-
- jmps macro there
- jmp short there
- endm
-
- wptr equ word ptr
- bptr equ byte ptr
-
- sBegin DATA
- sEnd DATA
-
- sBegin CODE
-
- assumes CS,CODE
- assumes DS,DATA
-
- externFP PatBlt
-
- ;
- ; Draw a triangle using GID's PatBlit.
- ;
- ; This code was the source for the DIBTriangle and is left here
- ; as an example.
- ;
- ; There is a lot of duplication between the routines, but that is
- ; because they are meant to be stand-alond examples
- ;
- cProc Triangle,<FAR,PUBLIC>,<si,di>
- parmW hDC
- parmD lpPoints
-
- localD dummy
-
- localW wNextScan
- localW nScans ; # scans in first part of triangle
- localW curY ; current scan
- localW pLineToChange ; address of DDA struct that will
- ; be updated for the second part of
- ; triangle
-
- localV pts, %(3*(size POINT)) ; local (sorted) copy of points
- localV lineL, %(size DDASTRUC) ; DDA info for left line
- localV lineR, %(size DDASTRUC) ; DDA info for right line
- cBegin
-
- ;---------------------------------------------------------------------------
- ; Sort the points by increasing Y order. Points are assumed to be in device
- ; coordinates by now.
- ;---------------------------------------------------------------------------
- smov es, ss ; point es:di to pts buffer
- lea di, pts
-
- lds si, lpPoints ; point ds:si to input points
-
- lodsw ; get first point in cx, dx
- xchg cx, ax ;
- lodsw ;
- xchg dx, ax ; cx = X1 dx = Y1
-
- lodsw ; get second point in bx, ax
- xchg bx, ax ;
- lodsw ; bx = X2 ax = Y2
- xchg ax, bx ; ax = X2 bx = Y2
-
- cmp bx, dx ; sort so that (ax, bx) <= (cx, dx)
- jle @F ; if Y1 <= Y2 then we're fine
- xchg ax, cx ; swap Y1 and Y2
- xchg bx, dx ; swap X1 and X2
- @@:
- cmp bx, [si+2] ; is (ax, bx) min coordinate?
- jle @F
-
- movsw ; copy smallest point to buffer
- movsw ;
- jmps trisort10 ; copy remainder to buffer
-
- @@:
- stosw ; copy smallest point to buffer
- xchg ax, bx ;
- stosw ;
-
- lodsw ; get third point in (ax, bx)
- xchg ax, bx
- lodsw
- xchg ax, bx ; ax = X3 bx = Y3
-
- cmp bx, dx ; sort so that (ax, bx) <= (cx, dx)
- jle trisort10 ; if Y1 <= Y2 then we're fine
- xchg ax, cx ; swap Y1 and Y2
- xchg bx, dx ; swap X1 and X2
-
- trisort10:
- stosw ; copy middle point to buffer
- xchg ax, bx ;
- stosw ;
-
- xchg ax, cx ; copy largest point to buffer
- stosw ;
- xchg ax, dx ;
- stosw ;
-
- EndTriSort:
-
- ;---------------------------------------------------------------------------
- ; Initialize the DDA structures so that we can fill between lineL and lineR.
- ;---------------------------------------------------------------------------
-
- smov ds, ss ; point DS to stack
- lea si, pts ; point DS:SI to points
-
- lodsw ; get first two points:
- xchg bx, ax ; (dx,ax) = pt 2, (bx,cx) = pt 1
- lodsw ;
- xchg cx, ax ;
- lodsw ;
- xchg dx, ax ;
- lodsw ;
-
- mov curY, cx ; start at top scan of triangle
-
- lea si, lineL ; point SI to left DDA structure
- lea di, lineR ; point DI to right DDA structure
- cmp dx, bx ; is X2 > X1 ?
- jle @F ; no, we chose correctly
- xchg si, di ; switch left/right pointers
-
- @@:
- mov pLineToChange, si ; remember which DDA structure will
- ; need to be updated at the cut.
-
- call TriInitDDA ; fill in left DDA structure
- mov nScans, ax ; save # scans to first endpoint
-
- push si
- lea si, pts ; point DS:SI to points
- lodsw ; get first & third points:
- xchg bx, ax ; (dx,ax) = pt 3, (bx,cx) = pt 1
- lodsw ;
- xchg cx, ax ;
- add si, size POINT ; skip middle point
- lodsw ;
- xchg dx, ax ;
- lodsw ;
- pop si
-
- xchg si, di ; fill in right DDA structure
- call TriInitDDA ;
-
- ;---------------------------------------------------------------------------
- ; Walk the DDAs of the left and right lines, which are pointed to by SI and
- ; BX respectively. For each scan call the routine that plots the scanline.
- ;---------------------------------------------------------------------------
-
- xchg si, di ; SI = left line, DI = right line
- mov bx, di ; BX = right line
-
- TriRenderPiece:
- mov cx, nScans ; setup loop count
- jcxz TriNextPiece ; if current piece is
-
- TriRenderPieceLoop:
- push cx
- push bx
- mov ax, [si].pixCur ; Tell output routine to fill [ax,dx)
- mov dx, [bx].pixCur ;
- mov cx, curY ; on scanline cx
- mov bx, hDC ; ** pass in hDC for now...
- call OutScan ;
- pop bx
-
- mov cx, 2 ; two structures to update
-
- UpdateDDAs:
- xchg si, bx ; alternate between two structures
-
- mov ax, [si].pixXinc ; get X increment in a register
- or ax, ax ; is line vertical?
- jz EndOfDDAThing ; yes, no need to update DDA
-
- cmp [si].pixSlope, 0 ; is DX > DY?
- jz DoDDADXMajor ; yes, handle appropriately
-
- cmp [si].pixError, 0 ; is the error > 0
- jle AddToError ; no, just add to error term
- add [si].pixCur, ax ; add X increment to current pixel
- mov ax, [si].pixErrReset ; update error term
- add [si].pixError, ax ;
- jmps EndOfDDAThing ; we're done with DDA now
- AddToError:
- mov ax, [si].pixRem ; add to error term
- add [si].pixError, ax ;
- jmps EndOfDDAThing ; we're done with DDA now
-
- DoDDADXMajor:
- push bx ;
- push cx ;
- mov cx, ax ; put pixXinc in cx for now
- mov dx, [si].pixError ; put error in dx for now
- mov ax, [si].pixErrReset ; update error term
- add dx, ax ;
- mov ax, [si].pixCur ; ax will have pixCur
- add ax, cx ; update current position
- mov bx, [si].pixRem ; bx will have pixRem
- DXMajorLoop:
- cmp dx, 0 ; is error <= 0?
- jg DoneDXMajorLoop ; no, so we're done
- add ax, cx ; pixCur += pixXinc
- add dx, bx ; pixError += pixRem
- jmps DXMajorLoop ; keep going
- DoneDXMajorLoop:
- mov [si].pixError, dx ; save values back in structure
- mov [si].pixCur, ax ;
- pop cx ;
- pop bx ;
- EndOfDDAThing:
- loop UpdateDDAs
-
- inc curY ; move to next scanline
-
- pop cx ; restore scan count
- loop TriRenderPieceLoop ; fill rest of triangle
-
- TriNextPiece:
- cmp pLineToChange, 0 ; if 0 we're done
- je TriDone ;
-
- push si ; save left line
- push bx
-
- lea si, pts + size POINT ; point si to second point
- lodsw ; get second & third points:
- xchg bx, ax ; (dx,ax) = pt 3, (bx,cx) = pt 2
- lodsw ;
- xchg cx, ax ;
- lodsw ;
- xchg dx, ax ;
- lodsw ;
-
- mov si, pLineToChange ; point to DDA that will change
- call TriInitDDA ; and initialize for next line
- mov nScans, ax ;
- pop bx ;
- pop si ;
- mov pLineToChange, 0 ; signal this is last iteration
- jmp TriRenderPiece ;
-
- TriDone:
- cEnd
-
- ; Fill in DDA structure pointed to by DS:SI with line from (bx,cx) - (dx, ax)
- ; return DY in ax
- cProc TriInitDDA,<NEAR>,<si,di>
- cBegin
- ; Compute DX and DY, while preserving X values
- sub ax, cx
- xchg di, ax
- mov cx, dx
- sub cx, bx
-
- ; at this point the registers are as follows:
- ; di = DY cx = DX
- ; dx = iPtCur+1.X bx = iPtCur.X
-
- ; set the pixXinc
- xor ax, ax ; assume zero
- jcxz @F ; if it is great
- inc ax ; nope, assume it's positive
- or cx, cx ; is sign bit set?
- jns @F ; no, we chose correctly
- neg ax ; flip pixXinc
- neg cx ; force DX positive
- @@:
-
- ; Note: we don't need to check DY since the triangle code always passes in
- ; ax >= cx
-
- mov [si].pixXinc, ax ; save X increment in structure
- mov [si].pixCur, bx ; save pixCur in structure
- mov dx, di ; save DY in dx
-
- ; compute pixSlope (0 if DY > DX, non-zero otherwise)
- xor ax, ax ; assume DY > DX
- mov bx, 1 ; assume error roundup is 1
- cmp cx, di ; check if DY is > DX
- jg @F ; yup, we picked correctly
- not ax ; nope, set pixSlope
- xchg cx, di ; swap DX and DY
- or di, di ; if minor axis >= 0 then error
- jns @F ; roundup is okay
- xor bx, bx ; nope, clear error roundoff
- @@:
- mov [si].pixSlope, ax
-
- shl di, 1 ; double minor axis length
-
- mov [si].pixRem, di
- sub di, cx
- add di, bx
- mov [si].pixError, di
- sub di, bx
- sub di, cx
- mov [si].pixErrReset, di
-
- mov ax, dx ; return DY
- cEnd
-
- ; draw line segment [ax,dx) on scanline cx on hDC in bx
- cProc OutScan,<NEAR>,<si,di>
- cBegin
- push bx ; hDC
- push ax ; X
- push cx ; Y
- sub dx, ax
- inc dx
- push dx ; nWidth
- mov ax, 1
- push ax ; nHeight
- mov ax, 00F0h
- push ax ; PATCOPY
- mov ax, 0021h
- push ax
- cCall PatBlt ; use PatBlt to draw scanline
- cEnd
-
- ;
- ; This triangle code writes directly into the DIB memory
- ;
- ;
- ; WARNING: Known Bug:
- ;
- ; This code does not clip, and if it is asked to draw outside of image,
- ; it will try and usually cause GP Fault
- ;
- ; Clip points before calling this routine (or add clipping)
- ;
- ; adding clipping is left as an excercise for the reader.
- ;
-
- cProc DIBTriangle,<FAR,PUBLIC>,<si,di>
- parmD lpbi
- parmD lpPoints
- parmW crBrush
-
- localW wcrossflag ; set to 1 if sel crossing on next scan
- localW fnOutScan ; scanline output function
- localW wNextScan ; # of bytes to next scan line
- localW nScans ; # scans in first part of triangle
- localW curY ; current scan
- localW pLineToChange ; address of DDA struct that will
- ; be updated for the second part of
- ; triangle
-
- localV pts, %(3*(size POINT)) ; local (sorted) copy of points
- localV lineL, %(size DDASTRUC) ; DDA info for left line
- localV lineR, %(size DDASTRUC) ; DDA info for right line
- cBegin
-
- ;---------------------------------------------------------------------------
- ; Sort the points by increasing Y order. Points are assumed to be in device
- ; coordinates by now.
- ;---------------------------------------------------------------------------
- smov es, ss ; point es:di to pts buffer
- lea di, pts
-
- lds si, lpPoints ; point ds:si to input points
-
- lodsw ; get first point in cx, dx
- xchg cx, ax ;
- lodsw ;
- xchg dx, ax ; cx = X1 dx = Y1
-
- lodsw ; get second point in bx, ax
- xchg bx, ax ;
- lodsw ; bx = X2 ax = Y2
- xchg ax, bx ; ax = X2 bx = Y2
-
- cmp bx, dx ; sort so that (ax, bx) <= (cx, dx)
- jle @F ; if Y1 <= Y2 then we're fine
- xchg ax, cx ; swap Y1 and Y2
- xchg bx, dx ; swap X1 and X2
- @@:
- cmp bx, [si+2] ; is (ax, bx) min coordinate?
- jle @F
-
- movsw ; copy smallest point to buffer
- movsw ;
- jmps ctrisort10 ; copy remainder to buffer
-
- @@:
- stosw ; copy smallest point to buffer
- xchg ax, bx ;
- stosw ;
-
- lodsw ; get third point in (ax, bx)
- xchg ax, bx
- lodsw
- xchg ax, bx ; ax = X3 bx = Y3
-
- cmp bx, dx ; sort so that (ax, bx) <= (cx, dx)
- jle ctrisort10 ; if Y1 <= Y2 then we're fine
- xchg ax, cx ; swap Y1 and Y2
- xchg bx, dx ; swap X1 and X2
-
- ctrisort10:
- stosw ; copy middle point to buffer
- xchg ax, bx ;
- stosw ;
-
- xchg ax, cx ; copy largest point to buffer
- stosw ;
- xchg ax, dx ;
- stosw ;
-
- cEndTriSort:
-
- ;---------------------------------------------------------------------------
- ; Initialize the DDA structures so that we can fill between lineL and lineR.
- ;---------------------------------------------------------------------------
-
- smov ds, ss ; point DS to stack
- lea si, pts ; point DS:SI to points
-
- lodsw ; get first two points:
- xchg bx, ax ; (dx,ax) = pt 2, (bx,cx) = pt 1
- lodsw ;
- xchg cx, ax ;
- lodsw ;
- xchg dx, ax ;
- lodsw ;
-
- mov curY, cx ; start at top scan of triangle
-
- lea si, lineL ; point SI to left DDA structure
- lea di, lineR ; point DI to right DDA structure
- cmp dx, bx ; is X2 > X1 ?
- jle @F ; no, we chose correctly
- xchg si, di ; switch left/right pointers
-
- @@:
- mov pLineToChange, si ; remember which DDA structure will
- ; need to be updated at the cut.
-
- call TriInitDDA ; fill in left DDA structure
- mov nScans, ax ; save # scans to first endpoint
-
- push si
- lea si, pts ; point DS:SI to points
- lodsw ; get first & third points:
- xchg bx, ax ; (dx,ax) = pt 3, (bx,cx) = pt 1
- lodsw ;
- xchg cx, ax ;
- add si, size POINT ; skip middle point
- lodsw ;
- xchg dx, ax ;
- lodsw ;
- pop si
-
- xchg si, di ; fill in right DDA structure
- call TriInitDDA ;
-
- ;---------------------------------------------------------------------------
- ; Walk the DDAs of the left and right lines, which are pointed to by SI and
- ; BX respectively. For each scan call the routine that plots the scanline.
- ;---------------------------------------------------------------------------
-
- xchg si, di ; SI = left line, DI = right line
- mov bx, di ; BX = right line
-
- les di,lpbi
- mov ax,curY ; get y value of first scan line
- call tri_init
-
- ;;; mov ax,lpBuf.sel ; get segment of buffer
- ;;; mov es,ax ; into ES
- ;;; mov di,lpBuf.off ; lpbuf in ES:DI
-
- cTriRenderPiece:
- mov cx, nScans ; setup loop count
- jcxz cTriNextPiece ; if current piece is
-
- cTriRenderPieceLoop:
- push cx
-
- mov ax, [si].pixCur ; Tell output routine to fill [ax,dx)
- mov dx, [bx].pixCur ;
- ;;;;;;;;mov cx, curY ; on scanline cx
-
- cmp ax, dx ; Make sure AX <= DX
- jle @f
- xchg ax, dx ; swap point and wall pointers if not
- xchg bx, si ;
- @@:
- ;;;;;;;;arg lpBuf
- ;;;;;;;;arg <cx>
- ;;;;;;;;arg <ax> ;[bx].pixcur
- ;;;;;;;;arg <dx> ;[si].pixcur
- ;;;;;;;;arg crBrush
- push bx
- call [fnOutScan]
- pop bx
- ;;;;;;;; cCall DIBOutScan
-
- mov cx, 2 ; two structures to update
-
- cUpdateDDAs:
- xchg si, bx ; alternate between two structures
-
- mov ax, [si].pixXinc ; get X increment in a register
- or ax, ax ; is line vertical?
- jz cEndOfDDAThing ; yes, no need to update DDA
-
- cmp [si].pixSlope, 0 ; is DX > DY?
- jz cDoDDADXMajor ; yes, handle appropriately
-
- cmp [si].pixError, 0 ; is the error > 0
- jle cAddToError ; no, just add to error term
- add [si].pixCur, ax ; add X increment to current pixel
- mov ax, [si].pixErrReset ; update error term
- add [si].pixError, ax ;
- jmps cEndOfDDAThing ; we're done with DDA now
- cAddToError:
- mov ax, [si].pixRem ; add to error term
- add [si].pixError, ax ;
- jmps cEndOfDDAThing ; we're done with DDA now
-
- cDoDDADXMajor:
- push bx ;
- push cx ;
- mov cx, ax ; put pixXinc in cx for now
- mov dx, [si].pixError ; put error in dx for now
- mov ax, [si].pixErrReset ; update error term
- add dx, ax ;
- mov ax, [si].pixCur ; ax will have pixCur
- add ax, cx ; update current position
- mov bx, [si].pixRem ; bx will have pixRem
- cDXMajorLoop:
- cmp dx, 0 ; is error <= 0?
- jg cDoneDXMajorLoop ; no, so we're done
- add ax, cx ; pixCur += pixXinc
- add dx, bx ; pixError += pixRem
- jmps cDXMajorLoop ; keep going
- cDoneDXMajorLoop:
- mov [si].pixError, dx ; save values back in structure
- mov [si].pixCur, ax ;
- pop cx ;
- pop bx ;
- cEndOfDDAThing:
- loop cUpdateDDAs
-
- inc curY ; move to next scanline
-
- pop cx ; restore scan count
- loop cTriRenderPieceLoop ; fill rest of triangle
-
- cTriNextPiece:
- cmp pLineToChange, 0 ; if 0 we're done
- je cTriDone ;
-
- push si ; save left line
- push bx
-
- lea si, pts + size POINT ; point si to second point
- lodsw ; get second & third points:
- xchg bx, ax ; (dx,ax) = pt 3, (bx,cx) = pt 2
- lodsw ;
- xchg cx, ax ;
- lodsw ;
- xchg dx, ax ;
- lodsw ;
-
- mov si, pLineToChange ; point to DDA that will change
- call TriInitDDA ; and initialize for next line
- mov nScans, ax ;
- pop bx ;
- pop si ;
- mov pLineToChange, 0 ; signal this is last iteration
- jmp cTriRenderPiece ;
-
- cTriDone:
- cEnd
-
- if 1
- ;--------------------------Private-Routine-------------------------------;
- ; tri_init
- ;
- ; init the bitmap pointer ES:DI to point to proper scan
- ;
- ; Entry:
- ; ES:DI --> BITMAPINFO
- ; AX - start scanline
- ; SS:BP --> frame of DibTriangle
- ; Return:
- ; ES:DI points to start of first scan
- ; carry clear
- ; SS:BP --> frame of DIBTriangle
- ; Error Returns:
- ; carry set
- ; Registers Preserved:
- ; none
- ; Registers Destroyed:
- ; AX,BX,CX,DX,DS,ES,SI,DI,FLAGS
- ; Calls:
- ; exclude !!!
- ; History:
- ; Mon 26-Mar-1990 -by- Todd Laney [ToddLa]
- ; Stole it from KenSy
- ;-----------------------------------------------------------------------;
- assumes ds,nothing
- assumes es,nothing
- ifdef DEBUG
- public tri_init
- endif
-
- tri_init proc near
- xor dx,dx
- mov wcrossflag,dx
-
- mov dx,wptr es:[di].biWidth ; compute DWORD aligned
- add dx,3 ; ...scan width and save it
- and dx,not 3
- mov wNextScan,dx
-
- sub ax,wptr es:[di].biHeight ; Y = biHeight-1-Y
- inc ax
- neg ax
-
- add di,wptr es:[di].biSize
- add di,256 * 4 ; !!!assumes full color table
-
- mul dx ; DX:AX = offset start of scan
- add di,ax
- adc dx,0 ; DX:DI --> start of scan
-
- mov cx,__AHSHIFT ; do the selector tile stuff
- shl dx,cl
- mov ax,es
- add ax,dx
- mov es,ax ; ES:DI --> start of scan
-
- mov ax,CodeOFFSET DIBOutScan
- mov fnOutScan,ax
-
- tri_init_success:
- clc
- ret
-
- tri_init_fail:
- stc
- ret
-
- tri_init endp
-
-
- endif
-
-
- ;--------------------------Private-Routine-------------------------------;
- ; DIBOutScan
- ;
- ; output a single scanline of a triangle [ax,dx)
- ;
- ; Entry:
- ; AX - start X
- ; DX - end X (inclusive!)
- ; ES:DI - points to start of scanline
- ; SS:BP - Frame of Custom Triangle
- ; Return:
- ; ES:DI advanced to start of next scan
- ; Error Returns:
- ; none
- ; Registers Preserved:
- ; BX,DS,ES,SI,DI
- ; Registers Destroyed:
- ; AX,CX,DX,FLAGS
- ; Calls:
- ; none
- ; History:
- ; Mon 26-Mar-1990 -by- Todd Laney [ToddLa]
- ; Stole it from KenSy
- ;-----------------------------------------------------------------------;
- assumes ds,nothing
- assumes es,nothing
-
- ifdef DEBUG
- public diboutscan ;; for debugging
- endif
-
- DIBOutScan proc near
- mov cx,__WinFlags
- test cx,WF_CPU286
- jnz DIBOutScan286
- errn$ DIBOutScan386
-
- DIBOutScan386:
-
- ; 386 specific version goes here.
- ; for now, just use 286 version
- ;
- DIBOutScan286:
- mov cx,dx
- sub cx,ax ; calc delta
- inc cx ; cx is # of pels
-
- cmp wcrossflag,1
- je DIBOutCrossing
- mov dx,di
- sub dx,wNextScan ; advance to next scan
- jb DIBOutNextCrossing ; we have a seg crossing on next line
- DIBOutSafe:
-
- add di,ax ; point ES:DI to start of scan
- mov al,bptr crBrush ; get color to store in al and ah
- mov ah,al
-
- shr cx,1
- rep stosw
- adc cl,cl
- rep stosb
-
- mov di,dx ; advance to next scan
- ret
-
- DIBOutNextCrossing:
- ;; next scan line has a crossing...
- mov wcrossflag,1
- mov dx,di ; save old (unmodified) di
- ; don't update es:di, yet
- jmps DIBOutSafe
-
-
-
- DIBOutCrossing:
-
- ;; there is a crossing somewhere in the current scanline.
- mov wcrossflag,0 ; we've handled it...
-
- mov cx,dx
- ;; ax is start
- ;; cx is end
- ;; di is old offset
-
- ;;;
- mov dx,di
- mov di,wNextScan
- sub di,dx ; di = wNextScan - old offset
-
- sub dx,wNextScan
-
-
-
- ;;; still need to check for the old 'off-by-one' errors
-
- ;; di is wNextScan - old offset
- ;; dx is new offset
- ; es is old sel
- ; es - __AHINCR is new sel
-
- ; V-------------------wNextScan-------------------V
- ;
- ; V--wNextScan - old_offset----V----old_offset----V
- ;
- ;
- ; |-----------------------------------------------|
- ;
- ; current scan line es-__AHINCR:dx-->
- ; |----------------------------|------------------|
- ; es:0---^
- ;
- ; |-----------------------------------------------|
- ;
- ;
- ; Three posibilities:
- ;
- ; 1 |----------------------------|------------------|
- ; ^ ^
- ; Start End
- ;
- ; 2 |----------------------------|------------------|
- ; ^ ^
- ; Start End
- ;
- ; 3 |----------------------------|------------------|
- ; ^ ^
- ; Start End
- ;
-
- cmp ax,di ; is start > di?
- jg DIBOutCase2
- cmp cx,di ; is end <= di?
- jle DIBOutCase3
- ; else:
- ; case 1
- ; do from es:0 -> end - di first
- sub cx,di
- mov di,0 ; by definition, start of seg
-
- push ax ; save start
- mov al,bptr crBrush
- mov ah,al
- shr cx,1
- rep stosw
- adc cl,cl
- rep stosb
-
-
- ; now do from es-__AHINCR:dx+start -> ffff
- mov ax,es
- sub ax,__AHINCR
- cmp ax,lpbi.sel ; compare to buffer
- jl DIBOutFirstpop ; don't mod if before buffer
- mov es,ax
-
- pop ax ; restore start
-
- mov di,dx
- add di,ax ; es:di ->start
-
- mov cx,dx ; get # to move:
- add cx,ax ; add start offset to line
- not cx ; get # to end
-
- inc cx ; fill in last byte
-
- ; move the data...
- mov al,bptr crBrush
- mov ah,al
- shr cx,1
- rep stosw
- adc cl,cl
- rep stosb
-
- mov di,dx ; setup next line...
- sub di,wNextScan
-
- ret
-
-
- DIBOutCase3:
- mov di,dx ; we won't cross... do it
- mov dx,es
- sub dx,__AHINCR
- cmp dx,lpbi.sel ; compare to buffer
- jl DIBOutFirst ; don't mod if before buffer
- mov es,dx
-
- mov dx,di
- sub dx,wNextScan ; setup next scan line
- ; (can't have another seg crossing)
-
- sub cx,ax ; get count
- inc cx
-
- jmp DIBOutSafe
-
- DIBOutCase2:
- ; we won't cross, but special calcs are needed to get next sel
-
- sub cx,ax
- inc cx ; cx is # of pels
-
- sub ax,di ; start - offset
- mov di,ax ; point ES:DI to start of scan
-
- mov al,bptr crBrush ; get color to store in al and ah
- mov ah,al
-
- shr cx,1
- rep stosw
- adc cl,cl
- rep stosb
-
- ; fall through...
-
- DIBOutScanWrap:
- sub dx,wNextScan ; point to next scan line
- mov di,dx
- mov ax,es
- sub ax,__AHINCR
- cmp ax,lpbi.sel ; compare to buffer
- jl DIBOutFirst ; don't mod if before buffer
- mov es,ax
- DIBOutFirst:
- ret
- DIBOutFirstpop:
- pop ax
- ret
-
- DIBOutScan endp
-
-
- ;---------------------------Public-Routine------------------------------;
- ; hmemcpy
- ;
- ; copy memory
- ;
- ; Entry:
- ; lpSrc HPSTR to copy from
- ; lpDst HPSTR to copy to
- ; cbMem DWORD count of bytes to move
- ;
- ; NOTE: overlapped copies will work iff lpSrc.sel == lpDst.sel
- ; [This is a lie. They will always work.]
- ;
- ; Returns:
- ; destination pointer
- ; Error Returns:
- ; None
- ; Registers Preserved:
- ; BP,DS,SI,DI
- ; Registers Destroyed:
- ; AX,BX,CX,DX,FLAGS
- ; Calls:
- ; nothing
- ;-----------------------------------------------------------------------;
-
- cProc hmemcpy,<FAR,PASCAL,PUBLIC,NODATA>,<>
- ; ParmD lpDst
- ; ParmD lpSrc
- ; ParmD cbMem
- cBegin <nogen>
- mov ax,__WinFlags
- test ax,WF_CPU286
- jz fmemcpy386
- jmp FAR PTR fmemcpy286
- cEnd <nogen>
-
- cProc fmemcpy386,<FAR,PASCAL,PUBLIC,NODATA>,<ds>
- ParmD lpDst
- ParmD lpSrc
- ParmD cbMem
- cBegin
- .386
- push edi
- push esi
- cld
-
- mov ecx,cbMem
- jecxz mc386_exit
-
- movzx edi,di
- movzx esi,si
- lds si,lpSrc
- les di,lpDst
- ;
- ; calculate differance of pointers in "selector" space
- ;
- mov ax,si ; DX:AX = lpSrc
- mov dx,ds
-
- mov bx,es ; BX = selector of ptr B
-
- mov cx,__AHSHIFT ; number of selector bits per 64K 'segment'
- shr dx,cl ; linearize ptr A
- shr bx,cl ; linearize ptr B
- ;
- ; DX and BX contain normalized selectors
- ;
- sub ax,di
- sbb dx,bx ; do long subtraction.
-
- mov ecx,cbMem
-
- or dx,dx
- jns mc_copy_forward
-
- std
- add edi,ecx
- add esi,ecx
-
- sub edi,4
- sub esi,4
-
- push ecx
- shr ecx,2 ; get count in DWORDs
- rep movs dword ptr es:[edi], dword ptr ds:[esi]
- db 67H ; Fix strange 386 bug
- add edi,3
- add esi,3
- pop ecx
- and ecx,3
- rep movs byte ptr es:[edi], byte ptr ds:[esi]
- db 67H ; Fix strange 386 bug
- jmp mc386_exit
-
- mc_copy_forward:
- push ecx
- shr ecx,2 ; get count in DWORDs
- rep movs dword ptr es:[edi], dword ptr ds:[esi]
- db 67H
- pop ecx
- and ecx,3
- rep movs byte ptr es:[edi], byte ptr ds:[esi]
- db 67H
- nop
- mc386_exit:
- cld
- pop esi
- pop edi
- mov dx,lpDst.sel ; return destination address
- mov ax,lpDst.off
- .286
-
- ; return to .286 mode for cEnd and 286 version
- ;
-
- cEnd
-
- cProc fmemcpy286,<FAR,PASCAL,PUBLIC,NODATA>,<ds,si,di>
- ParmD lpDst
- ParmD lpSrc
- ParmD cbMem
- cBegin
- mov cx,cbMem.lo ; CX holds count
- or cx,cbMem.hi ; or with high word
- jnz @f
- jmp empty_copy
- @@:
- lds si,lpSrc ; DS:SI = src
- les di,lpDst ; ES:DI = dst
- ;
- ; calculate differance of pointers in "selector" space
- ;
- mov ax,si ; DX:AX = lpSrc
- mov dx,ds
-
- mov bx,es ; BX = selector of ptr B
-
- mov cx,__AHSHIFT ; number of selector bits per 64K 'segment'
- shr dx,cl ; linearize ptr A
- shr bx,cl ; linearize ptr B
- ;
- ; DX and BX contain normalized selectors
- ;
- sub ax,di
- sbb dx,bx ; do long subtraction.
-
- mov cx,cbMem.lo
-
- or dx,dx
- jns forward_copy ; difference is positive, so copy forward
-
- ; see if the blocks intersect: is source + count > dest?
- ; equivalently, is source-dest + count > 0 ?
- ; sub ax,cx
- ; sbb dx,0
- ; jnc next ; This looks wrong. Recheck!
-
- add ax,cx
- adc dx,cbMem.hi
- jc reverse_copy ; carry, so >0, thus they do hit.
-
- forward_copy:
- jmp next
-
- reverse_copy:
- ; first, we have to set ds:si and es:di to the _ends_ of the blocks
-
- sub cx,2
- sbb cbMem.hi,0 ; subtract 2 from (long) count
-
- xor ax,ax
- add si,cx
- adc ax,cbMem.hi
-
- push cx
- mov cx,__AHSHIFT
- shl ax,cl
- pop cx
- mov bx,ds
- add ax,bx ; advance DS
- mov ds,ax
-
- xor ax,ax
- add di,cx
- adc ax,cbMem.hi
-
- push cx
- mov cx,__AHSHIFT
- shl ax,cl
- pop cx
- mov bx,es
- add ax,bx ; advance ES
- mov es,ax
-
- add cx,2
- adc cbMem.hi,0 ; restore count
- ;
- ; DS:SI += Count
- ; ES:DI += Count
- ; While Count != 0 Do
- ; Num = MIN(Count,SI+1,DI+1)
- ; Reverse Copy "Num" Bytes from DS:SI to ES:DI
- ; (SI -= Num, DI -= Num)
- ; Count -= Num
- ; If Count == 0 Then
- ; BREAK
- ; If SI == 0xFFFF Then
- ; DS -= __AHINCR
- ; If DI == 0xFFFF Then
- ; ES -= __AHINCR
- ;
- next_r:
- mov ax,si
-
- sub ax,di
- sbb bx,bx
- and ax,bx
- add ax,di ; AX = MIN(SI, DI)
-
- xor bx,bx
- add ax,2 ; AX = Num = MIN(SI+2,DI+2)
- adc bx,0 ; bx==1 if exactly 64k
-
- test cbMem.hi,-1 ; is high word not zero?
- jnz @f ; at least 64k to go
-
- sub ax,cx
- sbb bx,bx
- and ax,bx
- add ax,cx ; AX = Num = MIN(Count,SI+2,DI+2)
- adc bx,0
-
- @@:
- xchg ax,cx
- sub ax,cx ; Count -= Num
- sbb cbMem.hi,bx
-
- std
- shr bx,1
- rcr cx,1 ; if bx==1, then cx ends up 0x8000
- jnc @f
- inc si ; adjust pointers for byte move
- inc di
- movsb ; move first byte, if necessary
- dec si ; realign pointers
- dec di
- @@:
- rep movsw
- cld
-
- mov cx,ax ; restore cx
- or ax,cbMem.hi
-
- jz done ; If Count == 0 Then BREAK
-
- cmp si,-2 ; if SI wraps, update DS
- jnz @f
- ;
- mov ax,ds
- sub ax,__AHINCR
- mov ds,ax ; update DS if appropriate
- @@:
- cmp di,-2 ; if DI wraps, update ES
- jnz next_r
- ;
- mov ax,es
- sub ax,__AHINCR
- mov es,ax ; update ES if appropriate
- jmp next_r
-
- ;
- ; While Count != 0 Do
- ; If (Count + SI > 65536) OR (Count + DI > 65536) Then
- ; Num = Min(65536-SI, 65536-DI)
- ; Else
- ; Num = Count
- ; Copy "Num" Bytes from DS:SI to ES:DI (SI += Num, DI += Num)
- ; Count -= Num
- ; If Count == 0 Then
- ; BREAK
- ; If SI == 0 Then
- ; DS += __AHINCR
- ; If DI == 0 Then
- ; ES += __AHINCR
- ;
- next:
- mov ax,cx
- dec ax
-
- mov ax,di
- not ax ; AX = 65535-DI
-
- mov dx,si
- not dx ; DX = 65535-SI
-
- sub ax,dx
- sbb bx,bx
- and ax,bx
- add ax,dx ; AX = MIN(AX,DX) = MIN(65535-SI,65535-DI)
-
- ; problem: ax might have wrapped to zero
-
- test cbMem.hi,-1
- jnz plentytogo ; at least 64k still to copy
-
- dec cx ; this is ok, since high word is zero
- sub ax,cx
- sbb bx,bx
- and ax,bx
- add ax,cx ; AX = MIN(AX,CX)
- inc cx
-
- plentytogo:
- xor bx,bx
- add ax,1 ; AX = Num = MIN(count,65536-SI,65536-DI)
- ; we must check the carry here!
- adc bx,0 ; BX could be 1 here, if CX==0 indicating
- ; exactly 64k to copy
- xchg ax,cx
- sub ax,cx ; Count -= Num
- sbb cbMem.hi,bx
-
- shr bx,1
- rcr cx,1 ; if bx==1, then cx ends up 0x8000
- rep movsw
- jnc @f
- movsb ; move last byte, if necessary
- @@:
- mov cx,ax ; put low word of count back in cx
- or ax,cbMem.hi
-
- jz done ; If Count == 0 Then BREAK
-
- or si,si ; if SI wraps, update DS
- jnz @f
- ;
- mov ax,ds
- add ax,__AHINCR
- mov ds,ax ; update DS if appropriate
- @@:
- or di,di ; if DI wraps, update ES
- jnz next
- ;
- mov ax,es
- add ax,__AHINCR
- mov es,ax ; update ES if appropriate
- jmp next
- ;
- ; Restore registers and return
- ;
- done:
- empty_copy:
- mov dx,lpDst.sel ; return destination address
- mov ax,lpDst.off
- cEnd
-
-
-
- sEnd CODE
- end
-